home *** CD-ROM | disk | FTP | other *** search
/ CU Amiga Super CD-ROM 24 / CU Amiga Magazine's Super CD-ROM 24 (1998)(EMAP Images)(GB)(Track 1 of 2)[!][issue 1998-07].iso / CUCD / Programming / SWI / source / lib / help.pl < prev    next >
Encoding:
Text File  |  1997-10-13  |  6.0 KB  |  241 lines

  1. /*  $Id: help.pl,v 1.11 1997/10/13 10:07:58 jan Exp $
  2.  
  3.     Copyright (c) 1990 Jan Wielemaker. All rights reserved.
  4.     jan@swi.psy.uva.nl
  5.  
  6.     Purpose: Give online help
  7. */
  8.  
  9. :- module(online_help,
  10.     [ help/1
  11.     , help/0
  12.     , apropos/1
  13.     ]).
  14.  
  15. :- use_module(library(helpidx)).
  16.  
  17. /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  18. This module  defines the  online  help  facility of   SWI-Prolog.   It
  19. assumes  (Prolog) index file  at library(help_index)   and  the actual
  20. manual  at library(online_manual).   Output  is piped through  a  user
  21. defined pager, which defaults to `more'.
  22.  
  23. BUGS:
  24. If the pager  is quit prematurely Prolog will  abort  on  noticing the
  25. broken pipe.
  26. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  27.  
  28. %    help/0
  29.  
  30. help :-
  31.     help(help/1).
  32.  
  33. %    help(+Subject)
  34. %    Display online help on specified subject.
  35.  
  36. help(What) :-
  37.     give_help(What).
  38.  
  39. %    apropos(Pattern)
  40. %    Give a list of subjects that might be appropriate.
  41.  
  42. apropos(What) :-
  43.     give_apropos(What).
  44.  
  45. give_help(Name/Arity) :- !,
  46.     predicate(Name, Arity, _, From, To), !,
  47.     show_help(Name/Arity, [From-To]).
  48. give_help(Section) :-
  49.     user_index(Index, Section), !,
  50.     section(Index, _, From, To),
  51.     show_help(Section, [From-To]).
  52. give_help(Function) :-
  53.     atom(Function),
  54.     concat('PL_', _, Function),
  55.     function(Function, From, To), !,
  56.     show_help(Function, [From-To]).
  57. give_help(Name) :-
  58.     findall(From-To, predicate(Name, _, _, From, To), Ranges),
  59.     Ranges \== [], !,
  60.     show_help(Name, Ranges).
  61. give_help(What) :-
  62.     format('No help available for ~w~n', What).
  63.  
  64. %    show_help(+ListOfRanges)
  65. %    Pipe specified ranges of the manual through the user defined pager
  66.  
  67. :- dynamic asserted_help_tmp_file/1.
  68.  
  69. help_tmp_file(X) :-
  70.     asserted_help_tmp_file(X), !.
  71. help_tmp_file(X) :-
  72.     tmp_file(manual, X),
  73.     asserta(asserted_help_tmp_file(X)).
  74.  
  75. write_ranges_to_file(Ranges, Outfile) :-
  76.     online_manual_stream(Manual),
  77.     help_tmp_file(Outfile),
  78.     open(Outfile, write, Output),
  79.     show_ranges(Ranges, Manual, Output),
  80.     close(Manual),
  81.     close(Output).
  82.  
  83. show_help(Title, Ranges) :-
  84.     current_predicate(_, show_help_hook(_,_)),
  85.     write_ranges_to_file(Ranges, TmpFile),
  86.     user:show_help_hook(Title, TmpFile).
  87. show_help(_, Ranges) :-
  88.     clause(running_under_emacs_interface, _), 
  89.     running_under_emacs_interface, !,
  90.     write_ranges_to_file(Ranges, Outfile),
  91.     call_emacs('(view-file-other-window "~w")', [Outfile]).
  92. show_help(_, Ranges) :-
  93.     \+ feature(pipe, true), !,
  94.     online_manual_stream(Manual),
  95.     show_ranges(Ranges, Manual, user_output).
  96. show_help(_, [Start-End]) :-
  97.     End - Start > 4000, !,
  98.     find_manual(Manual),
  99.     find_pager(Pager),
  100.     plbite_flags(Flags),
  101.     sformat(Cmd, 'pl-bite ~w ~d:~d ~a | ~a',
  102.         [Flags, Start, End, Manual, Pager]),
  103.     shell(Cmd).    
  104. show_help(_, Ranges) :-
  105.     online_manual_stream(Manual),
  106.     pager_stream(Pager),
  107.     show_ranges(Ranges, Manual, Pager),
  108.     close(Manual),
  109.     close(Pager).
  110.  
  111. plbite_flags('-e') :-
  112.     feature(write_help_with_overstrike, true), !.
  113. plbite_flags('').
  114.  
  115. show_ranges([], _, _) :- !.
  116. show_ranges([From-To|Rest], Manual, Pager) :-
  117.     stream_position(Manual, _, '$stream_position'(From, 0, 0)),
  118.     Range is To - From,
  119.     copy_chars(Range, Manual, Pager),
  120.     nl(Pager),
  121.     show_ranges(Rest, Manual, Pager).
  122.  
  123. copy_chars(N, From, To) :-
  124.     get0(From, C0),
  125.     copy_chars(N, From, To, C0).
  126.  
  127. copy_chars(0, _, _, _) :- !.
  128. copy_chars(N, _, To, _) :-
  129.     0 =:= N mod 4096,
  130.     flush_output(To),
  131.     fail.
  132. copy_chars(N, From, To, C) :-
  133.     get0(From, C1),
  134.     (   C1 == 8,            % backspace
  135.         \+ feature(write_help_with_overstrike, true)
  136.     ->  get0(From, C2),
  137.         NN is N - 3,
  138.         copy_chars(NN, From, To, C2)
  139.     ;   put_printable(To, C),
  140.         NN is N - 1,
  141.         copy_chars(NN, From, To, C1)
  142.     ).
  143.  
  144. put_printable(_, 12) :- !.
  145. put_printable(_, -1) :- !.
  146. put_printable(To, C) :-
  147.     put(To, C).
  148.  
  149. online_manual_stream(Stream) :-
  150.     find_manual(Manual),
  151.     open(Manual, read, Stream).
  152.  
  153. pager_stream(Stream) :-
  154.     find_pager(Pager),
  155.     open(pipe(Pager), write, Stream).
  156.  
  157. find_manual(Path) :-
  158.     absolute_file_name(library('MANUAL'), [access(read)], Path).
  159.  
  160. find_pager(Pager) :-
  161.     getenv('PAGER', Pager), !.
  162. find_pager(more).
  163.  
  164. /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  165. Set the write_help_with_overstrike feature.
  166. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  167.  
  168. set_overstrike_feature :-
  169.     feature(write_help_with_overstrike, _), !.
  170. set_overstrike_feature :-
  171.     getenv('TERM', xterm), !,
  172.     set_feature(write_help_with_overstrike, true).
  173. set_overstrike_feature :-
  174.     set_feature(write_help_with_overstrike, false).
  175.     
  176. :- initialization set_overstrike_feature.
  177.  
  178.  
  179. %    APROPOS
  180.  
  181. give_apropos(Atom) :-
  182.     ignore(predicate_apropos(Atom)),
  183.     ignore(function_apropos(Atom)),
  184.     ignore(section_apropos(Atom)).
  185.  
  186. apropos_predicate(Pattern, Name, Arity, Summary) :-
  187.     predicate(Name, Arity, Summary, _, _),
  188.     (   apropos_match(Pattern, Name)
  189.     ->  true
  190.     ;   apropos_match(Pattern, Summary)
  191.     ).
  192.  
  193. predicate_apropos(Pattern) :-
  194.     findall(Name-Arity-Summary,
  195.         apropos_predicate(Pattern, Name, Arity, Summary),
  196.         Names),
  197.     Names \== [],
  198.     forall(member(Name-Arity-Summary, Names),
  199.             format('~w/~w~t~30|~w~n', [Name, Arity, Summary])).
  200.  
  201. function_apropos(Pattern) :-
  202.     findall(Name, (function(Name, _, _),
  203.                apropos_match(Pattern, Name)), Names),
  204.     Names \== [],
  205.     forall(member(Name, Names),
  206.             format('Interface Function~t~30|~w()~n', Name)).
  207.  
  208. section_apropos(Pattern) :-
  209.     findall(Index-Name, (section(Index, Name, _, _),
  210.                apropos_match(Pattern, Name)), Names),
  211.     Names \== [],
  212.     forall(member(Index-Name, Names),
  213.             (user_index(Index, UserIndex),
  214.             format('Section ~w~t~30|"~w"~n', [UserIndex, Name]))).
  215.  
  216. apropos_match(A, B) :-
  217.     '$apropos_match'(A, B).            % C defined for performance
  218.  
  219. user_index(List, Index) :-
  220.     is_list(List), !,
  221.     to_user_index(List, S),
  222.     name(Index, S).
  223. user_index(List, Index) :-
  224.     to_system_index(Index, List).
  225.  
  226. to_user_index([], "").
  227. to_user_index([A], S) :- !,
  228.     name(A, S).
  229. to_user_index([A|B], S) :-
  230.     name(A, S0),
  231.     append(S0, "-", S1),
  232.     append(S1, Rest, S),
  233.     to_user_index(B, Rest).
  234.  
  235. to_system_index(A-B, I) :- !,
  236.     to_system_index(A, C),
  237.     integer(B),
  238.     append(C, [B], I).
  239. to_system_index(A, [A]) :-
  240.     integer(A).
  241.